home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / sbprolog / amiga / v3_1 / sbp3_1e.lzh / OBJECT.PL < prev    next >
Text File  |  1991-10-31  |  2KB  |  76 lines

  1. /* From the book PROLOG PROGRAMMING IN DEPTH
  2.    by Michael A. Covington, Donald Nute, and Andre Vellino.
  3.    Copyright 1988 Scott, Foresman & Co.
  4.    Non-commercial distribution of this file is permitted. */
  5. /* Modified for Quintus Prolog by Andreas Siebert */
  6.  
  7. /* OBJECT.PL */
  8. /* Sample of object-oriented programming */
  9. /* Adapted from Stabler (1986) */
  10.  
  11. /* Variable names beginning with underscores,
  12.    such as _c, are those that are not used further
  13.    in the computation. Their names look like
  14.    anonymous variables but have more mnemonic value. */
  15.  
  16. /* load the math library */
  17. :- ensure_loaded(library(math)).
  18.  
  19. object(spaceship(X_Velocity,Y_Velocity,Mass),
  20.            [
  21.             (kinetic_energy(E) :- E is 0.5 * Mass *
  22.                  (X_Velocity*X_Velocity + Y_Velocity*Y_Velocity)),
  23.             (speed(S) :- sqrt(X_Velocity*X_Velocity + Y_Velocity*Y_Velocity),S),
  24.             description('a space ship')
  25.            ]).
  26.  
  27. object(enterprise(_,_,_),
  28.     [description('a federation star ship')]).
  29.  
  30. object(klingon(_,_,_),
  31.     [description('an enemy star ship')]).
  32.  
  33. isa(klingon(X_Velocity,Y_Velocity,Mass),
  34.                         spaceship(X_Velocity,Y_Velocity,Mass)).
  35. isa(enterprise(X_Velocity,Y_Velocity,Mass),
  36.                         spaceship(X_Velocity,Y_Velocity,Mass)).
  37.  
  38. send(Object, Message) :-
  39.     isa_hierarchy(Object, Object1),
  40.     object(Object1,MethodList),
  41.     get_method(Message,MethodList,Method),
  42.     call(Method).
  43.  
  44. get_method(Message,[FirstMethod|_],Method) :-
  45.     fact_or_rule(Message,FirstMethod,Method),
  46.     !.
  47. get_method(Message,[_|Rest],Method) :-
  48.     get_method(Message,Rest,Method).
  49.  
  50. fact_or_rule(Message,Message,true).
  51. fact_or_rule(Message,(Message:-Body),Body).
  52.  
  53. isa_hierarchy(Object,Object).
  54. isa_hierarchy(Object,Object1) :-
  55.     isa(Object,Object2),
  56.     isa_hierarchy(Object2,Object1).
  57.  
  58. /* Starting query */
  59.  
  60.  
  61. :-  nl,
  62.     nl,
  63.     write('Sending energy message to Enterprise...'),
  64.     send(enterprise(20,30,40),kinetic_energy(E)),
  65.     nl,
  66.     write('Energy is '),
  67.     write(E),
  68.     nl,
  69.     write('Sending description message to Klingon...'),
  70.     send(klingon(_xv,_yv,_m),description(D)),
  71.     nl,
  72.     write('Klingon is '),
  73.     write(D),
  74.     nl,
  75.     nl.
  76.